TableGetFloatByString Subroutine

private subroutine TableGetFloatByString(valueIn, tab, keyIn, keyOut, valueOut)

returns a float from column defined by keyOut corresponding to
valueIn (string) contained in column defined by keyIn. Arguments: valueIn input value tab table to search in keyIn defines header of the column of the input value keyOut defines header of the column of the output value

The method to match input value is 'exact' by definition, no need to include optional arguments

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: valueIn
type(Table), intent(in) :: tab
character(len=*), intent(in) :: keyIn
character(len=*), intent(in) :: keyOut
real(kind=float), intent(out) :: valueOut

Variables

Type Visibility Attributes Name Initial
type(Column), public, POINTER :: colIn
type(Column), public, POINTER :: colOut
logical, public :: foundValue
integer(kind=short), public :: i
character(len=100), public :: string
character(len=100), public :: string2

Source Code

SUBROUTINE TableGetFloatByString &
!
( valueIn, tab, keyIn, keyOut, valueOut )

! Module used:
USE StringManipulation, ONLY: &
! imported routines:
StringCompact, StringToUpper, StringToFloat, ToString

USE LogLib, ONLY : &
! Imported Routines:
Catch

USE ErrorCodes, ONLY : &
! Imported parameters:
unknownOption


IMPLICIT NONE

! Function arguments
! Scalar arguments with intent(in):
CHARACTER (LEN = *),  INTENT (IN) :: valueIn
CHARACTER (LEN = *),  INTENT (IN) :: keyIn
CHARACTER (LEN = *),  INTENT (IN) :: keyOut

! Type defined arguments with intent (in):
TYPE (Table), INTENT (IN) :: tab

! Scalar arguments with intent(out):
REAL (KIND = float), INTENT (OUT) :: valueOut

! Local scalars:
TYPE (Column), POINTER :: colIn
TYPE (Column), POINTER :: colOut
INTEGER (KIND = short) :: i
CHARACTER (LEN = 100)  :: string
CHARACTER (LEN = 100)  :: string2
LOGICAL                :: foundValue

!------------end of declaration------------------------------------------------
!inizialization
foundValue = .FALSE.

!find columns to be processed
DO i = 1, tab % noCols
  string = StringCompact (StringToUpper (tab % col (i) % header) ) 
  IF ( string == StringToUpper(keyIn) ) THEN
    colIn => tab % col (i) !colIn is an alias of the input column
  ELSE IF ( string == StringToUpper(keyOut) ) THEN  
    colOut => tab % col (i) !colOut is an alias of the output column
  END IF 
END DO

!find match for valueIn
string =  StringToUpper ( valueIn )
DO i = 1, tab % noRows
    string2 = StringToUpper ( colIn % row (i) )
    IF ( string == string2 ) THEN
    foundValue = .TRUE.
    valueOut = StringToFloat (colout % row (i))
    END IF
END DO
IF ( .NOT. foundValue ) THEN
    CALL Catch ('error', 'TableLib',   &
        TRIM ( TRIM(valueIn) ) // ' not found in table: ' ,  &
		argument = tab % id )
END IF

RETURN
END SUBROUTINE TableGetFloatByString